home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / brklyprl.lha / Emulator / Benchmarks / differen.pl < prev    next >
Encoding:
Text File  |  1989-04-14  |  923 b   |  37 lines

  1.  
  2. /* Copyright (C) 1988, 1989 Herve' Touati, Aquarius Project, UC Berkeley */
  3.  
  4. %    differen (times10,divide10,log10,ops8)
  5. %    These 4 examples are from Warren's thesis
  6.  
  7. main :-
  8.     times10(I1),
  9.     d(I1,x,D1),
  10.     write(D1), nl,
  11.     divide10(I2),
  12.     d(I2,x,D2),
  13.     write(D2), nl,
  14.     log10(I3),
  15.     d(I3,x,D3),
  16.     write(D3), nl,
  17.     ops8(I4),
  18.     d(I4,x,D4),
  19.     write(D4), nl.
  20.  
  21. d(U+V,X,DU+DV) :- !, d(U,X,DU), d(V,X,DV).
  22. d(U-V,X,DU-DV) :- !, d(U,X,DU), d(V,X,DV).
  23. d(U*V,X,DU*V+U*DV) :- !, d(U,X,DU), d(V,X,DV).
  24. d(U/V,X,(DU*V-U*DV)/(^(V,2))) :- !, d(U,X,DU), d(V,X,DV).
  25. d(^(U,N),X,DU*N*(^(U,N1))) :- !, integer(N), N1 is N - 1, d(U,X,DU).
  26. d(-U,X,-DU) :- !, d(U,X,DU).
  27. d(exp(U),X,exp(U)*DU) :- !, d(U,X,DU).
  28. d(log(U),X,DU/U) :- !, d(U,X,DU).
  29. d(X,X,1).
  30. d(C,X,0).
  31.  
  32. times10( ((((((((x*x)*x)*x)*x)*x)*x)*x)*x)*x ).
  33. divide10( ((((((((x/x)/x)/x)/x)/x)/x)/x)/x)/x ).
  34. log10( log(log(log(log(log(log(log(log(log(log(x)))))))))) ).
  35. ops8( (x+1)*((^(x,2)+2)*(^(x,3)+3)) ).
  36.  
  37.